home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Gigarom 1
/
Gigarom Macintosh Archives (Quantum Leap)(CDRM1080320)(1993).iso
/
FILES
/
MID
/
Util
/
MIDI.a.cpt
/
midi.a
next >
Wrap
Text File
|
1987-03-26
|
18KB
|
704 lines
* MIDI.a - assembly language routines callable from MPW C
*
* The following routines are provided for communicating with a MIDI interface
* through the Macintosh's serial ports. If you want to call them from
* MPW Pascal, simply declare them with the EXTERNAL; C; directives.
* NOTE NOTE NOTE: You MUST put this module in a segment that remains fixed for
* the duration of the program (like ARes in a MacApp program). These routines
* mess with the interrupts, and contain code that can be jumped to
* asynchronously.
*
* SCCInitA(clockRate,txBuffer,rxBuffer) -Initialize port A to
* int clockRate; communicate with MIDI.
* Ptr txBuffer,rxBuffer;
*
* SCCInitB(clockRate,txBuffer,rxBuffer) -Initialize port B to
* int clockRate; communicate with MIDI.
* Ptr txBuffer,rxBuffer;
*
* TxMIDI(port,outByte) -Transmit one byte to MIDI port
* int port,outByte;
*
* int
* RxMIDI(port) -Recieve one byte from MIDI port (or -1 if none)
* int port;
*
* Boolean
* MIDIBusy(port) -Returns true if still transmitting, else false
* int port;
*
* MIDIEnable(port,mode) -Sets MIDI mode: enabled, disabled,
* int port,mode; echoA or echoB
*
* SCCRstA() -Resets SCC and restores interrupts
*
* SCCRstB() -Resets SCC and restores interrupts
CASE OBJECT ;Communicate with C
OPT NOCLR
* Fetch the following equates for serial chip addresses and offsets
* from SysEqu.a
*
* SCCRd SCC base read address [pointer]
* SCCWr SCC base write address [pointer]
* Lvl2DT Interrupt level 2 dispatch table [32 bytes]
* aData offset for A channel data
* aCtl offset for A channel control
* bData offset for B channel data
* bCtl offset for B channel control
* txBE SCC transmit buffer empty
* CurrentA5 current value of A5 [pointer]
Include 'SysEqu.a'
Include 'Traps.a'
Lvl2Int EQU $0200
TxAIntOffset EQU 16
RxAIntOffset EQU 24
SACondOffset EQU 28
TxBIntOffset EQU 0
RxBIntOffset EQU 8
SBCondOffset EQU 12
PortA EQU 0
PortB EQU 1
Disabled EQU 0
EchoA EQU 1
EchoB EQU 2
Enabled EQU 3
* Macro for silly do-nothing instruction that allows the SCC chip
* to settle down
MACRO
delay
move.l (sp),(sp)
ENDM
* Macro for writing SCC control ports, assuming a0
* is already set up to point to them
MACRO
ToScc ®Ptr,&message
move.b ®Ptr,(a0) ;pointer for SCC reg
delay
move.b &message,(a0) ;send byte to SCC reg
delay
ENDM
* The following record template, Q (for queue, get it?) is a very important
* data structure in this set of routines. It completely defines a data queue,
* including housekeeping variables and the SCC addresses pertaining to the
* queue. Each port can have a transmit queue and a receive queue, so there
* may be four of these data structures in all. The total size is dependent
* on the size of the non-relocatable blocks delivered in the SCCInit routines,
* where the queues are initialized.
Q: RECORD {Queue}
Empty ds.b 1 ;1 if queue is empty, 0 otherwise
Enable ds.b 1 ;0:disabled,3:enabled,1:echo to A, 2:echo to B
ByteIn ds.w 1 ;index to next cell in
ByteOut ds.w 1 ;index to next cell out
Size ds.w 1 ;size of following queue
CtlAddr ds.l 1 ;address of control register for this queue
DataAddr ds.l 1 ;address of data register for this queue
OldInt ds.l 1 ;old interrupt vector
Queue ds.b 1 ;but it can be as big as you want
ENDR
Globals: RECORD ;--------------------MIDI Globals---------------------
ChnReset ds.w 1 ;SCC channel reset select
OldSACondInt ds.l 1
OldSBCondInt ds.l 1
TxAQueue ds.l 1 ;transmitted data queue,port A
RxAQueue ds.l 1 ;received data queue, port A
TxBQueue ds.l 1 ;transmitted data queue,port B
RxBQueue ds.l 1 ;received data queue, port B
ENDR
ENTRY (RxAIntHand,RxBIntHand):CODE
ENTRY (TxAIntHand,TxBIntHand):CODE
ENTRY (SACondHand,SBCondHand):CODE
PROC
EXPORT (SCCInitA,SCCInitB):CODE
BRANCH SHORT
WITH Globals
* These are the initialization routines which should be called
* when you initialize quickdraw and the various managers
* Call SCCInitA to use the modem port, and SCCInitB to use the printer port
* The calling sequence is:
* SCCInitA(clockRate,txBuffer,rxBuffer)
* or SccInitB(clockRate,txBuffer,rxBuffer)
* where:
*
* clockRate is an integer; the legal values are 500,
* 1000, or 2000, depending on whether the external clock
* provided by the MIDI interface is 500kHz, 1MHz, or 2MHz.
*
* txBuffer is the address of a buffer for the transmitted data;
* this must be a pointer to a non-relocatable block provided
* by the Memory Manager. It should be of sufficient size to
* handle the biggest data block that you might want to send
* at one time; remember that the Macintosh can fill up the
* transmission buffer much more quickly than it can be
* transmitted at the MIDI baud rate.
*
* rxBuffer is the address of a buffer for the received data; comments
* that were made about txBuffer apply to this buffer also.
* Note: registers d0,a0,a1 are not preserved - they need not be if called
* from MPW C
Frame RECORD {LinkReg}
LinkReg ds.l 1
Return ds.l 1
clockRate ds.l 1
TxBuffer ds.l 1
RxBuffer ds.l 1
ENDR
WITH Frame
MACRO
SetUpQ &port,&io ;&port = A/B; &io = Tx/Rx
; Set up queue address (it must point at the first location
; after all of the houskeeping variables, which are kept at
; the beginning of the non-relocatable block
move.l &io.Buffer(a6),a0 ;pointer to non-reloc. block in a0
_GetPtrSize ;leaves size in d0
sub.l #Q,a0 ;a0 points to beginning of queue
move.l a0,&io&port.Queue ;save queue pointer
add.w #Q,d0 ;Q is a negative offset
move.w d0,Q.Size(a0)
move.l &io&port.Queue,r&io.Queue
;Now initalize the queue housekeeping variables
IF &io = 'Tx' THEN
move.l SCCWr,a1
ELSE
move.l SCCRd,a1
ENDIF
move.w #&port.Ctl,d0
lea (a1,d0),a0
move.l a0,Q.CtlAddr(r&io.Queue)
move.w #&port.Data,d0
lea (a1,d0),a0
move.l a0,Q.DataAddr(r&io.Queue)
clr Q.ByteIn(r&io.Queue) ;init flags and pointers
clr Q.ByteOut(r&io.Queue)
move.b #$ff,Q.Empty(r&io.Queue)
clr.b Q.Enable(r&io.Queue)
; Initialize interrupt vectors
move.l #Lvl2DT,a0 ;get dispatch table pointer
move.l &io&port.IntOffset(a0),Q.OldInt(r&io.Queue)
lea &io&port.IntHand,a1
move.l a1,&io&port.IntOffset(a0)
IF &io = 'Rx' THEN ;only do this once
lea S&port.CondHand,a1
move.l S&port.CondOffset(a0),OldS&port.CondInt ;save old address
move.l a1,S&port.CondOffset(a0)
ENDIF
ENDM
* Define some mnemonic names for the registers we use to address the queues
rTxQueue EQU a2
rRxQueue EQU a3
SCCInitA:
link a6,#0
movem.l rTxQueue/rRxQueue,-(sp)
move sr,-(sp) ;Save interrupts
ori #Lvl2Int,sr ;Disable interrupts
SetUpQ A,Tx
SetUpQ A,Rx
move.b #%10000000,ChnReset
bra.w SCCInit
SCCInitB:
link a6,#0
movem.l rTxQueue/rRxQueue,-(sp)
move sr,-(sp) ;Save interrupts
ori #Lvl2Int,sr ;Disable interrupts
SetUpQ B,Tx
SetUpQ B,Rx
move.b #%01000000,ChnReset
SCCInit:
move.l Q.CtlAddr(rRxQueue),a0
move.b (a0),d0 ;dummy read
delay
move.l Q.CtlAddr(rTxQueue),a0
;Reset channel
ToScc #9,ChnReset
;This is where you determine the external clock rate
;%01000100 = 500 kHz
;%10000100 = 1 MHz
;%11000100 = 2 MHz
cmp.l #500,clockRate(a6) ;is the argument 500kHz?
bne clk2000 ;no, try 2MHz
ToScc #4, #%01000100 ;16x clock, 1 stop bit
bra endclk
clk2000: cmp.l #2000,clockRate(a6)
bne clk1000 ;no, assume 1Mhz
ToScc #4, #%11000100 ;64x clock, 1 stop bit
bra endclk
clk1000: ToScc #4, #%10000100 ;32x clock, 1 stop bit
endclk: ToScc #1, #$00 ;No W/Req
ToScc #3, #$00 ;Turn off Rx
ToScc #5, #$00 ;Turn off Tx
ToScc #9, #$00 ;*Master interrupt disable
ToScc #11,#$28 ;Make TRxC clock source
ToScc #14,#$00 ;Disable BRGen
ToScc #3, #$c1 ;Enable Rx
ToScc #5, #$6a ;Enable Tx and drivers
ToScc #0, #$80 ;*Reset TxCRC
ToScc #15,#$08 ;Enable DCD int for mouse
ToScc #0, #$10 ;Reset EXT/STATUS
ToScc #0, #$10 ;Reset EXT/STATUS
ToScc #1, #$13 ;Enable interrupts
ToScc #9, #$0a ;Set master int enable
move (sp)+,sr ;Restore interrupts
movem.l (sp)+,rTxQueue/rRxQueue
unlk a6 ;Restore link register
rts ;and return
ENDWITH
ENDPROC
*
* This is the MPW C subroutine to transmit a MIDI byte of data.
* Calling convention:
* TxMIDI(port,outByte);
* Note: Registers d0,a0,a1 are not preserved; they need not be
* if called from MPW C
*
TxMIDI PROC EXPORT
Frame RECORD {LinkReg}
LinkReg ds.l 1
Return ds.l 1
port ds.l 1 ;MIDI port (0 = A, 1 = B)
outByte ds.l 1 ;Data byte to be transmitted (least sig. byte)
ENDR
WITH Globals
WITH Frame
link a6,#0 ;set frame pointer
move.l a2,-(sp)
move sr,-(sp) ;save interrupts
ori #Lvl2Int,sr ;disable interrupts
move.l TxAQueue,a0 ;in case port = A
move.l RxAQueue,a2
tst.l port(a6)
beq @3
move.l TxBQueue,a0
move.l RxBQueue,a2
@3
tst.b Q.Empty(a0) ;is TxQueue empty?
bne @TxQE ;if so, branch
move Q.ByteIn(a0),d0 ;if not, add byte to queue
move.l outByte(a6),d1 ;get longword containing data byte
move.b d1,(a0,d0) ;place byte in queue
addq #1,d0 ;update TxByteIn
cmp Q.Size(a0),d0
bne @1
clr d0
@1
move d0,Q.ByteIn(a0)
bra @Exit ;and exit
@TxQE:
move.l Q.CtlAddr(a2),a1 ;get SCC Read Control Address
btst.b #txBE,(a1) ;transmit buffer empty?
bne @FirstByte ;if so, branch
move Q.ByteIn(a0),d0 ;if not, add to queue
move.l outByte(a6),d1 ;get longword containing data byte
move.b d1,(a0,d0) ;place byte in queue
addq #1,d0 ;update index
cmp Q.Size(a0),d0
bne @2
clr d0
@2
move d0,Q.ByteIn(a0)
clr.b Q.Empty(a0) ;reset queue empty flag
bra @Exit ;and exit
@FirstByte:
move.l Q.DataAddr(a0),a1 ;get SCC Write Data address
delay
move.l outByte(a6),d1 ;get longword containing data byte
move.b d1,(a1) ;write data to SCC
delay
@Exit:
move (sp)+,sr ;restore interrupts
move.l (sp)+,a2
unlk a6 ;restore frame pointer
rts
ENDWITH
ENDWITH
ENDPROC
*
* This routine receives a byte of MIDI data. It returns an int data type;
* The byte is actually returned in the lower half of the returned int.
* Calling convention:
* inByte = RxMIDI(port);
* If no byte is available at the time the routine is called, -1 is returned.
* Note: registers d0,d1, and a1 are not preserved, as they need not be if
* called by MPW C.
*
RxMIDI FUNC EXPORT
Frame RECORD {LinkReg}
LinkReg ds.l 1
Return ds.l 1
port ds.l 1 ;MIDI port (0 = A, 1 = B)
ENDR
WITH Globals
WITH Frame
link a6,#0 ;set frame pointer
move sr,-(sp) ;save interrupts
ori #Lvl2Int,sr ;disable interrupts
move.l RxAQueue,a0 ;in case port = A
tst.l port(a6)
beq @3
move.l RxBQueue,a0
@3
tst.b Q.Empty(a0) ;any data available?
beq @1 ;if so, branch
move.l #-1,d0 ;if not, return -1
bra @Exit
@1
move Q.ByteOut(a0),d1 ;get index to byte out
clr.l d0 ;return data in d0
move.b Q.Queue(a0,d1),d0 ;get MIDI data
addq #1,d1 ;update index
cmp.w Q.Size(a0),d1
bne @2
clr.w d1
@2
move.w d1,Q.ByteOut(a0)
cmp.w Q.ByteIn(a0),d1 ;is queue empty?
bne @Exit ;if not, exit
move.b #$ff,Q.Empty(a0) ;if empty, set flag
@Exit:
move (sp)+,sr ;restore interrupts
unlk a6 ;restore frame pointer
rts ;return
ENDWITH
ENDWITH
ENDFUNC
MIDIBusy FUNC EXPORT
* This routine informs the program of the status of the transmit queue; it
* returns TRUE if the queue is not empty and FALSE if it is. The main purpose
* of this routine is to allow the calling program to check whether it is safe
* to call SCCRstA or SCCRstB.
* Boolean MIDIBusy(port);
* int port;
Frame RECORD {LinkReg}
LinkReg ds.l 1
Return ds.l 1
port ds.l 1 ;MIDI port (0 = A, 1 = B)
ENDR
WITH Globals
WITH Frame
link a6,#0 ;set frame pointer
move.l #-1,d0 ;set true (i.e. busy)
lea RxAQueue,a0 ;in case this is port A
lea TxAQueue,a1
tst.b port(a6)
beq @1
lea RxBQueue,a0
lea TxBQueue,a1
@1 tst.b Q.Empty(a1) ;is queue empty
beq @Exit ;if not, d0 is correct
;if we reach this point, the Tx queue is empty, but the SCC
;might still be busy transmitting a byte. Let's check.
move.l Q.CtlAddr(a0),a1
btst.b #txBE,(a1) ;transmit buffer empty?
beq @Exit ;if not, d0 is correct
clr.l d0 ;otherwise, set false
@Exit: unlk a6 ;restore frame pointer
rts
ENDWITH
ENDWITH
ENDFUNC
;The following routine sets the RxEnable flag; there are four modes in which
;a receive queue may be, Disabled (=0), Enabled, EchoA and EchoB. In the
;disabled state all received MIDI bytes are thrown away. in the enabled state
;they are placed in a queue for reading by RxMIDI. In the two echo modes,
;the received bytes are never returned to RxMIDI (i.e. they are not put in
;the queue), but they are automatically echoed either to the A or B port.
;Note: disabling the port has the effect of throwing away any bytes that may
;still remain in the receive queue.
; MIDIEnable(port,mode);
; int port,mode;
MIDIEnable PROC EXPORT
Frame RECORD {LinkReg}
LinkReg ds.l 1
Return ds.l 1
port ds.l 1 ;MIDI port (0 = A, 1 = B)
mode ds.l 1
ENDR
WITH Globals
WITH Frame
link a6,#0
move.l RxAQueue,a0 ;in case port = PortA
tst.l port(a6)
beq @1
move.l RxBQueue,a0
@1 move.l mode(a6),d0
move.b d0,Q.Enable(a0)
tst.b d0
bne @Exit ;if not disabled, our work is done
;otherwise, clear queue
move sr,-(sp) ;save interrupts
ori #Lvl2Int,sr ;disable interrupts
clr Q.ByteIn(a0) ;reset Rx queue variables
clr Q.ByteOut(a0)
move.b #$ff,Q.Empty(a0)
move (sp)+,sr ;restore interrupts
@Exit
unlk a6
rts
ENDWITH
ENDWITH
ENDPROC
;Note: In the following interrupt handling routines, the registers
;a0-a3 and d0-d3 are not preserved, since the Mac interrupt handler
;does this for us before calling these routines (see Inside Macintosh I-200)
;This is the interrupt routine for receiving a byte of MIDI data. It
;places the received byte in a circular queue to be accessed later
;by the application.
PROC
ENTRY (RxAIntHand,RxBIntHand):CODE
ENTRY (TxAIntHand,TxBIntHand):CODE
ENTRY (SACondHand,SBCondHand):CODE
WITH Globals
RxAIntHand:
move.l a5,-(sp) ;Might not be pointing to App. Globals
move.l CurrentA5,a5 ;so we can access globals
move.l RxAQueue,a2
bra RxIntHand
RxBIntHand:
move.l a5,-(sp) ;Might not be pointing to App. Globals
move.l CurrentA5,a5 ;so we can access globals
move.l RxBQueue,a2
RxIntHand:
;Remember: a0 points to control read, data read is at offset 4
clr.l d1
move.b 4(a0),d1 ;read data from SCC
delay
tst.b Q.Enable(a2) ;is receive disabled?
beq @Exit ;if so, simply throw away byte and go
cmp.b #EchoA,Q.Enable(a2) ;do we echo to port A?
bne @TestB
;call TxMIDI
move.l d1,-(sp) ;push byte
move.l #PortA,-(sp) ;push port number
bsr.w TxMIDI
addq.l #8,sp ;pop parameters
bra @Exit
@TestB cmp.b #EchoB,Q.Enable(a2) ;do we echo to port B?
bne @QueueUp ;if not, must save in queue
;call TxMIDI
move.l d1,-(sp) ;push byte
move.l #PortB,-(sp) ;push port number
bsr.w TxMIDI
addq.l #8,sp ;pop parameters
bra @Exit
@QueueUp move Q.ByteIn(a2),d0 ;get offset to next cell
move.b d1,(a2,d0) ;put byte in queue
clr.b Q.Empty(a2) ;reset queue empty flag
addq #1,d0 ;update index
cmp.w Q.Size(a2),d0
bne @1
clr.w d0
@1 move.w d0,Q.ByteIn(a2)
@Exit move.l (sp)+,a5
rts
;This is the interrupt routine for transmitting a byte of MIDI data.
;It checks to see if there is any data to send. If there is, it sends
;it to the SCC. If there isn't, it resets the txBE interrupt in the
;SCC and exits.
TxAIntHand:
move.l a5,-(sp) ;Might not be pointing to App. Globals
move.l CurrentA5,a5 ;so we can access globals
move.l TxAQueue,a2
bra TxIntHand
TxBIntHand:
move.l a5,-(sp) ;Might not be pointing to App. Globals
move.l CurrentA5,a5 ;so we can access globals
move.l TxBQueue,a2
TxIntHand:
tst.b Q.Empty(a2) ;is queue empty?
beq @1 ;if not branch
;Remember: a1 points to control write, data write is at offset 4
move.b #$28,(a1) ;if so, reset txBE interrupt
bra @Exit ;and exit
@1 move.w Q.ByteOut(a2),d0 ;get index to next data byte
move.b (a2,d0),4(a1) ;write data to SCC
addq #1,d0 ;update index
cmp.w Q.Size(a2),d0
bne @2
clr.w d0
@2 move.w d0,Q.ByteOut(a2)
move.w Q.ByteIn(a2),d1
cmp.w d0,d1 ;is TxQueue empty?
bne @Exit ;if not, exit
move.b #$ff,Q.Empty(a2) ;if so, set flag
@Exit:
move.l (sp)+,a5
rts ;and return
; Special condition interrupt handler; resets the input and output ports
SACondHand:
move.l SCCRd,a0
move #aData,d0
tst.b aData(a0) ;clear Rx buffer
move.l SCCWr,a0
move.b #$30,aCtl(a0) ;reset error
rts
SBCondHand:
move.l SCCRd,a0
tst.b bData(a0) ;clear Rx buffer
move.l SCCWr,a0
move.b #$30,bCtl(a0) ;reset error
rts
ENDWITH
ENDPROC
;These routines must be called when the application quits or the system
;will crash due to the interrupt handling pointers becoming invalid.
PROC
EXPORT (SCCRstA,SCCRstB):CODE
WITH Globals
SCCRstA:
move sr,-(sp) ;save interrupts
ori #$0300,sr ;disable interrupts
move.b #%10000000,ChnReset
;Restore old interrupts
move.l #Lvl2DT,a0 ;get dispatch table pointer
move.l OldSACondInt,SACondOffset(a0)
move.l RxAQueue,a1
move.l Q.OldInt(a1),RxAIntOffset(a0)
move.l TxAQueue,a1
move.l Q.OldInt(a1),TxAIntOffset(a0)
bra SCCReset ;with register a1 pointing to TxQueue
SCCRstB:
move sr,-(sp) ;save interrupts
ori #$0300,sr ;disable interrupts
move.b #%10000000,ChnReset
;Restore old interrupts
move.l #Lvl2DT,a0 ;get dispatch table pointer
move.l OldSBCondInt,SBCondOffset(a0)
move.l RxBQueue,a1
move.l Q.OldInt(a1),RxBIntOffset(a0)
move.l TxBQueue,a1
move.l Q.OldInt(a1),TxBIntOffset(a0)
SCCReset:
move.l Q.CtlAddr(a1),a0
ToScc #9,ChnReset ;Reset channel
ToScc #15,#$08 ;Enable DCD int
ToScc #0, #$10 ;Reset EXT/STATUS
ToScc #0, #$10 ;Reset EXT/STATUS
ToScc #1, #$01 ;Enable mouse interrupts
ToScc #9, #$0a ;Set master int enable
move (sp)+,sr ;restore interrupts
rts
ENDWITH
ENDPROC
END